home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / sbprolog / amiga / v3_1 / sbp3_1e.lzh / DREASON.PL < prev    next >
Text File  |  1991-10-31  |  4KB  |  142 lines

  1. /* From the book PROLOG PROGRAMMING IN DEPTH
  2.    by Michael A. Covington, Donald Nute, and Andre Vellino.
  3.    Copyright 1988 Scott, Foresman & Co.
  4.    Non-commercial distribution of this file is permitted. */
  5. /* Modified for Quintus Prolog by Andreas Siebert */
  6.  
  7. /* DREASON.PL */
  8. /* Defeasible Reasoner */
  9.  
  10. /*****************************************************
  11.  * This file will define the special operators and   *
  12.  * predicates used by a defeasible inference engine. *
  13.  * This file must be loaded before any other files   *
  14.  * containing defeasible rules, presumptions, or     *
  15.  * defeaters are loaded. Otherwise, Prolog will be   *
  16.  * unable to read these special representations.     *
  17.  *****************************************************/
  18.  
  19. :- unknown(_,fail).
  20.  
  21. init :- op(1100,fx,@),
  22.         op(900,fx,neg),
  23.         op(1100,xfx,:=),
  24.         op(1100,xfx,:^),
  25.     op(700,xfx,\=).
  26.  
  27. :- init.
  28.  
  29. /*
  30.  * To invoke the defeasible inference engine, put the
  31.  * operator @ in front of your goal. For example, the
  32.  * defeasible inference engine will be used to try to
  33.  * satisfy the goal ?- @ flies(X).
  34.  */
  35.  
  36. @(Condition) :- Condition =.. [',',First,Rest],
  37.                 !,
  38.                 @(First),
  39.                 @(Rest).
  40.  
  41. @(X\=Y) :- X=Y, !, fail.
  42. @(_\=_) :- !.
  43.  
  44. @(Goal) :- Goal =.. [P|_],
  45.        system(P),
  46.        !,
  47.        Goal.
  48.  
  49. @(Goal) :- Goal.
  50.  
  51. @(Goal) :- strict_rule(Goal,Condition),
  52.            @(Condition),
  53.            opposite(Goal,Contrary),
  54.            \+ Contrary.
  55.  
  56. @(Goal) :- (Goal:=Condition),
  57.            @(Condition),
  58.            opposite(Goal,Contrary),
  59.            \+ Contrary,
  60.            \+ defeat((Goal:=Condition)).
  61.  
  62. system('=').
  63. system('<').
  64. system('>').
  65. system('-').
  66. system('+').
  67. system('/').
  68. system('*').
  69.  
  70. strict_rule(true,_) :- !, fail.
  71. strict_rule(Goal,Condition) :- clause(Goal,Condition).
  72.  
  73. opposite(neg Clause,Clause) :- !.
  74. opposite(Clause,neg Clause).
  75.  
  76. /*
  77.  * defeat(DefeasibleRule)
  78.  *   succeeds if the opposite of the head of DefeasibleRule
  79.  *   succeeds, or if there is a competing absolute rule,
  80.  *   defeasible rule, or defeater whose body is defeasibly
  81.  *   derivable. For competing defeasible rules or defeaters,
  82.  *   the body of the competing rule must not be properly
  83.  *   included in the information required to satisfy the body
  84.  *   of DefeasibleRule.
  85.  */
  86.  
  87. defeat((Head:=_)) :-
  88.      opposite(Head,ContraryOfHead),
  89.      strict_rule(ContraryOfHead,Condition),
  90.      @(Condition).
  91.  
  92. defeat((Head:=Body)) :-
  93.      opposite(Head,ContraryOfHead),
  94.      (ContraryOfHead:=Condition),
  95.      not_more_informative(Body,Condition),
  96.      @(Condition).
  97.  
  98. defeat((Head:=Body)) :-
  99.      opposite(Head,ContraryOfHead),
  100.      (ContraryOfHead:^Condition),
  101.      not_more_informative(Body,Condition),
  102.      @(Condition).
  103.  
  104. not_more_informative(Clauses1,Clauses2) :-
  105.      \+ absolute_consequence(Clauses2,Clauses1).
  106.  
  107. not_more_informative(Clauses1,Clauses2) :-
  108.      absolute_consequence(Clauses1,Clauses2).
  109.  
  110. /*
  111.  * absolute_consequence(Goals,Premises)
  112.  *   succeeds if every member of Goals can be derived
  113.  *   from a knowledge base containing only the facts in
  114.  *   Premises plus the absolute rules in the actual
  115.  *   knowledge base.
  116.  */
  117.  
  118. absolute_consequence(Goals,Premises) :-
  119.      Goals =.. [',',First,Rest],
  120.      !,
  121.      absolute_consequence(First,Premises),
  122.      absolute_consequence(Rest,Premises).
  123.  
  124. absolute_consequence(true,_).
  125.  
  126. absolute_consequence(Goal,Premises) :-
  127.      belongs(Goal,Premises).
  128.  
  129. absolute_consequence(Goal,Premises) :-
  130.      strict_rule(Goal,Body),
  131.      \+ (Body = true),  /* there is no \= in Quintus Prolog */
  132.      absolute_consequence(Body,Premises).
  133.  
  134. belongs(Clause,Clause).
  135.  
  136. belongs(Clause,Conjunction) :-
  137.     Conjunction =.. [',',Clause,_].
  138.  
  139. belongs(_,Conjunction) :-
  140.      Conjunction =.. [',',_,RestOfConjunction],
  141.      belongs(_,RestOfConjunction).
  142.